home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
2.2
/
TerminalEmulators.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
36KB
|
1,343 lines
" NAME TerminalEmulators
AUTHOR tph@cs.man.ac.uk
FUNCTION VS100/VT100 etc emulators
ST-VERSIONS 2.2
PREREQUISITES
CONFLICTS
DISTRIBUTION world
VERSION 1.1
DATE 22 Jan 1989
SUMMARY TerminalEmulators
provides a number of `intelligent' terminal
emulators, including VS100 (large and small) and Newbury terminals.
The small VS100 emulator seems to provide a reasonable imitation of
a VT100 as well.
This goodie is known to work only with VI2.2 images. Some work will
be required to get it to function with earlier images. TPH
"!
'From Smalltalk-80, Version 2.2 of July 4, 1987 on 6 September 1987 at 2:20:00 pm'!
!Character class methodsFor: 'accessing untypeable characters'!
bell
"Answer the Character representing a bell."
^self value: 7! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:32:58 pm'!
!Character class methodsFor: 'accessing untypeable characters'!
null
"Answer the Character representing a null."
^self value: 0! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:33:03 pm'!
!CharacterScanner methodsFor: 'access'!
font: aFont
"Make the font used aFont."
font _ aFont! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:33:06 pm'!
!CharacterScanner methodsFor: 'access'!
outputMedium: aDisplayMedium
"Set the display medium to be used to aDisplayMedium."
outputMedium _ aDisplayMedium! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:33:14 pm'!
!CharacterScanner methodsFor: 'access'!
spaceWidth: aWidth
spaceWidth _ aWidth! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:33:18 pm'!
!CharacterScanner methodsFor: 'access'!
stopConditions
"Answer with the stop conditions."
^stopConditions! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:33:21 pm'!
!CharacterScanner methodsFor: 'access'!
text: aText
"Make the text used aText."
text _ aText! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:33:25 pm'!
!CharacterScanner methodsFor: 'access'!
textStyle: aTextStyle
"Make the textStyle used aTextStyle."
textStyle _ aTextStyle! !'From Smalltalk-80, Version 2.2 of July 4, 1987 on 5 September 1987 at 5:34:11 pm'!
!ExternalPort methodsFor: 'intialize-release'!
initializePort
receiveBuffer _ ByteArray new: 10240.
receiveSemaphore _ Semaphore new.
sendSemaphore _ Semaphore new.
Smalltalk addDependent: self! !Model subclass: #TermEmulator
instanceVariableNames: 'contents x y displayProcess serialPort numberOfColumns numberOfLines changedLines '
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
TermEmulator comment:
'I represent a model for a basic terminal emulator. Instances of me can be
used, together with an instance of TermEmulatorController and an instance
of TermEmulatorView, to provide a simple (dumb) terminal interface to the
underlying Unix system.
Instance variables:
contents An OrderedCollection of ByteArrays, used to contain the
actual characters represented by me.
x The current x location of the cursor.
y The current y location of the cursor.
displayProcess The process which runs asynchonously, which gets characters
from the input port.
serialPort The serial port currently being used.
numberOfColumns, numberOfLines -- the size of the (emulated) screen.
changedLines An Array of Boolean values, indicating which lines have been
changed. This is used to improve the performance, by ensuring
that the same line is not updated unnecessarily.
'!
!TermEmulator methodsFor: 'initialize-release'!
initialize
"Initialize the contents of the receiver. If this message is
overridden by a subclass, make use that the expression
'super initialize' is included."
self initializeLinesAndColumns.
self clear.
self home!
release
self close.
super release! !
!TermEmulator methodsFor: 'accessing'!
contentsAt: aLine
"Answer with the String which form the contents of the receiver
at aLine."
^contents at: aLine!
cursorLocation
"Answer with a point representing the current location of the cursor."
^x @ y!
numberOfColumns
"Answer with the number of columns of characters are represented
by the receiver."
^numberOfColumns!
numberOfLines
"Answer with the number of lines of characters are represented
by the receiver."
^numberOfLines!
serialPort
"Answer with the serial port to which the receiver is attached."
^serialPort! !
!TermEmulator methodsFor: 'port control'!
close
"If the serial port is open, close it."
(serialPort notNil and: [serialPort isOpen])
ifTrue: [serialPort removeDependent: self.
serialPort release.
serialPort close]!
reset
"Reset the serial port. Sometimes useful if a disaster occurs."
(serialPort notNil and: [serialPort isOpen])
ifTrue: [serialPort reset]! !
!TermEmulator methodsFor: 'character handling'!
displayCharacter: char
"Interpret char appropriately."
char isAlphaNumeric ifTrue: [
self processPrintingCharacter: char.
^self advanceCursor].
char = Character null ifTrue: [^self].
char = Character cr ifTrue: [^self processCRCharacter].
char = Character lf ifTrue: [^self processLFCharacter].
char = Character backspace ifTrue: [^self processBackspaceCharacter].
char = Character bell ifTrue: [^self processBellCharacter].
char = Character tab ifTrue: [^self processTabCharacter].
self processPrintingCharacter: char.
self advanceCursor!
displayCharacters
"This is where incoming characters are interpreted."
self changed: #cursor.
[serialPort atEnd] whileFalse: [
self displayCharacter: serialPort next asCharacter].
self changed: y.
1 to: numberOfLines do: [:eachLine |
(changedLines at: eachLine) ifTrue: [super changed: eachLine]].
changedLines atAllPut: false.
self changed: #cursor!
processBackspaceCharacter
"Deal with a backspace character."
x > 1 ifTrue: [x _ x - 1]!
processBellCharacter
"Deal with a bell character."
self changed: #flash!
processCRCharacter
"Deal with a Carriage Return (CR) character."
x _ 1!
processLFCharacter
"Deal with a Line Feed (LF) character."
self changed: y.
(y >= numberOfLines)
ifTrue: [self scroll]
ifFalse: [y _ y + 1].
Processor yield!
processPrintingCharacter: char
"The character char is assumed to be a printing character. Add
it to the model appropriately."
(contents at: y) at: x put: char asciiValue!
processTabCharacter
"Add one or more space characters to get the cursor to the next tab stop."
self processPrintingCharacter: Character space.
self advanceCursor.
x < (numberOfColumns - 8) ifTrue: [
[x isMultipleOf: 8] whileFalse: [
self processPrintingCharacter: Character space.
self advanceCursor]]! !
!TermEmulator methodsFor: 'display manipulation'!
advanceCursor
"Move the cursor one to the right, provided that we are
not already at the right-hand edge."
(x < numberOfColumns) ifTrue: [x _ x + 1]!
clear
"Clear the contents of the receiver."
contents _ OrderedCollection new: numberOfLines.
numberOfLines timesRepeat: [contents addLast:
(ByteArray new: numberOfColumns withAll: 32)].
changedLines _ Array new: numberOfLines withAll: false.!
home
"Return the cursor to the top left of the (simulated) screen."
x _ 1.
y _ 1!
scroll
"Scroll up the receiver by one line."
self changed: #scroll.
self scrollBy: 1.!
scrollBy: aNumber
"Scroll up the receiver aNumber lines."
(aNumber < numberOfLines) ifFalse: [^self clear].
aNumber timesRepeat: [
contents removeFirst.
contents addLast: (ByteArray new: numberOfColumns withAll: 32)].! !
!TermEmulator methodsFor: 'updating'!
changed: parameter
"Intercept this to ensure that multiple updates to the same
line are not carried out."
(parameter isKindOf: Number) ifTrue: [
^changedLines at: parameter put: true].
(parameter == #scroll) ifTrue: [
1 to: numberOfLines do: [:eachLine |
(changedLines at: eachLine) ifTrue: [super changed: eachLine]].
changedLines atAllPut: false].
super changed: parameter!
update: parameter
"Process a dependency message"
parameter == #closeBeforeSnapshot
ifTrue: [^displayProcess terminate].
parameter == #openAfterSnapshot
ifTrue: [^self startReceiveProcess].
parameter == #externalPortError
ifTrue: [self close.
^self changed: #externalPortError]! !
!TermEmulator methodsFor: 'private'!
initializeLinesAndColumns
"Set the default number of lines and columns."
self setLines: 24.
self setColumns: 80!
sendAll: aString
"Send out some of the user's input."
(serialPort notNil and: [aString size > 0])
ifFalse: [^false]
ifTrue: [^(serialPort sendBuffer: aString) ~~ nil]!
setColumns: aNumber
numberOfColumns _ aNumber!
setLines: aNumber
numberOfLines _ aNumber!
setSerialPort: aSerialPort
serialPort isNil ifFalse: [serialPort removeDependent: self].
serialPort _ aSerialPort .
serialPort addDependent: self.!
startReceiveProcess
"Fires up the background process that will run in parallel with the
user's input."
displayProcess _
[[serialPort notNil and: [serialPort isOpen]] whileTrue: [
serialPort receiveBuffer.
self displayCharacters]] newProcess.
displayProcess priority: Processor userSchedulingPriority.
displayProcess resume.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
TermEmulator class
instanceVariableNames: ''!
!TermEmulator class methodsFor: 'instance creation'!
new
"Answer with a new instance of the receiver."
^super new initialize!
openShell
"TermEmulator openShell."
TermEmulatorView
openOn: (self getTerminal)
label: 'Dumb TTY'!
openShell: aNumber
"TermEmulator openShell: 1."
TermEmulatorView
openOn: (self getTerminal: aNumber)
label: 'Dumb TTY'! !
!TermEmulator class methodsFor: 'private'!
getPort
"Get a shell port with any available number."
| port aShellNumber |
port _ nil.
aShellNumber _ 1.
[port isNil] whileTrue: [
port _ CShellPort open: aShellNumber.
aShellNumber _ aShellNumber + 1.
aShellNumber > 8 ifTrue: [
^self error: 'unable to open shell ', aShellNumber printString]].
^port!
getPort: aNumber
"Get a shell port corresponding to aNumber."
| port |
port _ CShellPort open: aNumber.
port isNil ifTrue: [^self error: 'unable to open shell ', aNumber printString].
^port!
getTerminal
"Get an instance of the receiver, with a shell port with
any available number attached to it."
^self new setSerialPort: (self getPort)!
getTerminal: aNumber
"Answer with an instance of the receiver connected to a
port given by aNumber."
^self new setSerialPort: (self getPort: aNumber)! !
View subclass: #TermEmulatorView
instanceVariableNames: 'style scanner '
classVariableNames: 'CharHeight '
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
TermEmulatorView comment:
'I represent the view of a simple terminal emulator.
style A TextStyle, which should be a fixed width text style.
scanner A CharacterScanner, used to display the characters. This
is a grubby hack, but used to try and improve the performance.
'!
!TermEmulatorView methodsFor: 'initialize-release'!
initialize
"Initialize the style used to display the contents."
self initializeScanner.
super initialize! !
!TermEmulatorView methodsFor: 'displaying'!
displayContents
"Display the contents of the model using the current text style."
self displaySafe: [
1 to: self model numberOfLines do: [:eachLine |
self reallyDisplayLine: eachLine]]!
displayCursor
"Display (or remove) the cursor."
self displaySafe: [
Display reverse: (self model cursorLocation * (7@CharHeight)
+ (-3@-12) + self insetDisplayBox topLeft
extent: 7@CharHeight)]!
displayLine: aNumber
"Display the line of the model indicated by aNumber."
self displaySafe: [self reallyDisplayLine: aNumber]!
displayScroll
"Copy the form up as in the scrolling operation."
Display
copy: (insetDisplayBox topLeft + (0@2)
extent: (insetDisplayBox width)@(model numberOfLines -1 * CharHeight))
from: (insetDisplayBox topLeft + (0@(2+CharHeight)))
in: Display
rule: Form over!
displayView
"Display the contents of the model and the cursor."
self displayContents.
self displayCursor!
reallyDisplayLine: aNumber
"Display the line of the model indicated by aNumber."
scanner clipRect: insetDisplayBox.
scanner destOrigin: (4 @ (aNumber - 1 * CharHeight + 2)) + insetDisplayBox topLeft.
scanner
scanCharactersFrom: 1
to: model numberOfColumns
in: (model contentsAt: aNumber)
rightX: insetDisplayBox right
stopConditions: scanner stopConditions
displaying: true! !
!TermEmulatorView methodsFor: 'updating'!
update: aParameter
"The model has changed, so update the display in some way."
aParameter == #flash ifTrue: [^self flash].
self topView isCollapsed ifFalse: [
aParameter == #cursor ifTrue: [^self displayCursor].
aParameter == #clear ifTrue: [^self displaySafe: [self clearInside]].
aParameter == #scroll ifTrue: [
^self displaySafe: [self displayScroll]].
(aParameter isKindOf: Number) ifTrue: [^self displayLine: aParameter]]! !
!TermEmulatorView methodsFor: 'controller access'!
defaultControllerClass
^TermEmulatorController! !
!TermEmulatorView methodsFor: 'private'!
flash
"Flash either the view once (if open) or the label three
times (if collapsed)."
self topView isCollapsed
ifTrue: [
3 timesRepeat: [self topView iconView flash]]
ifFalse: [
super flash]!
initializeScanner
"Initialize the character scanner used for displaying."
| font |
style _ TextStyle styleNamed: #fixed ifAbsent: [
^self error: 'fixed width text style not available'].
font _ style defaultFont.
scanner _ CharacterScanner new.
scanner combinationRule: Form over.
scanner destForm: Display.
scanner mask: nil.
scanner sourceY: 0.
scanner font: font.
scanner spaceWidth: (font widthOf: Character space).
scanner sourceForm: font glyphs.
scanner xTable: font xTable.
scanner height: font height.
scanner textStyle: style.
scanner outputMedium: Display.
scanner stopConditions: (Array new: 258).! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
TermEmulatorView class
instanceVariableNames: ''!
!TermEmulatorView class methodsFor: 'instance creation'!
openOn: aTermEmulator label: aString
"Create a new instance of the receiver with the model
being aTermEmulator and the label aString."
| size topView aView |
size _ (aTermEmulator numberOfColumns * 7 + 12) @
(aTermEmulator numberOfLines * CharHeight + 7).
topView _ StandardSystemView
model: aTermEmulator
label: aString
minimumSize: size.
topView maximumSize: size.
topView icon: (Icon constantNamed: #terminal).
topView borderWidth: 1.
topView borderColor: Form black.
aView _ self new model: aTermEmulator.
aView insideColor: Form white.
topView addSubView: aView in: (0@0 extent: 1@1) borderWidth: 1.
topView controller openNoTerminate.
aTermEmulator startReceiveProcess.
Cursor normal show.
Processor terminateActive! !
!TermEmulatorView class methodsFor: 'class initialization'!
initialize
"Initialize class variables."
"TermEmulatorView initialize."
CharHeight _ 13! !
TermEmulatorView initialize!
TermEmulator subclass: #IntelligentEmulator
instanceVariableNames: 'autoMargin autoLineFeed displayMode emphasis '
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
IntelligentEmulator comment:
'I add the functionality to support emulation of various types
of ''intelligent'' terminals (i.e. ones which support cursor movement, etc.).
I am an abstract superclass; subclasses of me should add the functionality
to interpret the incoming character stream.
Instance variables:
autoMargin A Boolean, indicating whether an automatic ''line-feed'' operation
is performed when the cursor hits the right-hand margin. Normally
true.
autoLineFeed A Boolean, indicating whether an automatic ''line-feed'' operation
is performed when a ''carriage return'' character is received.
Normally false.
displayMode An Integer, indicating which type of emphasis should be used for
incoming characters.
emphasis An OrderedCollection of ByteArrays, containing the emphasising
information for the corresponding characters.
'!
!IntelligentEmulator methodsFor: 'initialize-release'!
initialize
"Initialize various flags."
super initialize.
self resetDefaults! !
!IntelligentEmulator methodsFor: 'accessing'!
autoMargin: aBoolean
"Set the value of the automatic margin flag."
autoMargin _ aBoolean!
displayMode: anInteger
"Set the current display mode."
displayMode _ anInteger!
emphasisAt: aLine
"Answer with the Array which represents the emphasis on the line."
^emphasis at: aLine! !
!IntelligentEmulator methodsFor: 'character handling'!
processCRCharacter
"If the autoLineFeed flag is set, do an automatic LF after the CR."
super processCRCharacter.
autoLineFeed ifTrue: [self processLFCharacter]!
processPrintingCharacter: char
"Add the functionality required to handle emphasis."
super processPrintingCharacter: char.
(emphasis at: y) at: x put: displayMode! !
!IntelligentEmulator methodsFor: 'display manipulation'!
addLine
"Add a blank line at the position indicated by the cursor."
self addLines: 1!
addLines: aNumber
"Add aNumber blank lines at the position indicated by the cursor."
aNumber timesRepeat: [
contents add: (ByteArray new: numberOfColumns withAll: 32) beforeIndex: y.
emphasis add: (ByteArray new: numberOfColumns withAll: 0) beforeIndex: y.
contents removeLast.
emphasis removeLast].
y to: numberOfLines do: [:eachLine | self changed: eachLine]!
advanceCursor
"If the cursor is already at the right-hand edge, do an automatic
margin operation if the appropriate flag is set."
(x < numberOfColumns) ifTrue: [x _ x + 1. ^self].
autoMargin ifTrue: [
self processCRCharacter.
self processLFCharacter]!
clear
"Clear the display."
super clear.
emphasis _ OrderedCollection new.
numberOfLines timesRepeat: [
emphasis addLast: (ByteArray new: numberOfColumns withAll: 0)]!
clearEntireLine
"Clear the entire line."
(contents at: y) atAllPut: 32.
(emphasis at: y) atAllPut: 0.
self changed: y!
clearFromBeginningOfDisplay
"Clear the simulated screen from the start to the current location."
1 to: y - 1 do: [:eachLine |
contents at: eachLine put: (ByteArray new: numberOfColumns withAll: 32).
emphasis at: eachLine put: (ByteArray new: numberOfColumns withAll: 0).
self changed: eachLine].
self clearFromBeginningOfLine.!
clearFromBeginningOfLine
"Clear from the beginning of the line to the cursor."
1 to: x do: [:eachColumn |
(contents at: y) at: eachColumn put: 32.
(emphasis at: y) at: eachColumn put: 0].
self changed: y!
clearToEndOfDisplay
"Clear the simulated screen from the current location to the end."
self clearToEndOfLine.
y + 1 to: numberOfLines do: [:eachLine |
contents at: eachLine put: (ByteArray new: numberOfColumns withAll: 32).
emphasis at: eachLine put: (ByteArray new: numberOfColumns withAll: 0).
self changed: eachLine]!
clearToEndOfLine
"Clear from the current cursor position to the end of the line."
x to: numberOfColumns do: [:eachColumn |
(contents at: y) at: eachColumn put: 32.
(emphasis at: y) at: eachColumn put: 0].
self changed: y!
cursorDown: aNumber
"Move the cursor down the appropriate number of lines."
self moveToX: x y: y + aNumber!
cursorLeft: aNumber
"Move the cursor left (in a non-destructive manner) the
appropriate number of places."
self moveToX: x - aNumber y: y!
cursorRight: aNumber
"Move the cursor right (in a non-destructive manner) the
appropriate number of places."
self moveToX: x + aNumber y: y!
cursorUp: aNumber
"Move the cursor up the appropriate number of lines, unless the cursor
would overflow at the top."
self moveToX: x y: y - aNumber!
deleteCharacter
"Delete a character position at the current cursor location."
| line |
line _ (contents at: y).
x to: numberOfColumns - 1 do: [:eachPos |
line at: eachPos put: (line at: eachPos + 1)].
line at: numberOfColumns put: 32.
self changed: y!
deleteLine
"Delete the line at the position indicated by the cursor."
self deleteLines: 1!
deleteLines: aNumber
"Delete the line at the position indicated by the cursor."
aNumber timesRepeat: [
contents removeAtIndex: y.
emphasis removeAtIndex: y.
contents addLast: (ByteArray new: numberOfColumns withAll: 32).
emphasis addLast: (ByteArray new: numberOfColumns withAll: 0)].
y to: numberOfLines do: [:eachLine |
self changed: eachLine].!
doNothing
"Used when a sequence is defined, but not implemented here."
^self!
insertCharacter
"Insert a character position at the current cursor location."
| line |
line _ (contents at: y).
numberOfColumns to: x + 1 by: -1 do: [:eachPos |
line at: eachPos put: (line at: eachPos - 1)].
line at: x put: 32.
self changed: y!
moveToX: xLocation y: yLocation
"Position the cursor at the location given by xLocation and yLocation.
Ignore the command if the parameters are outside the allowable range."
(xLocation < 1 or: [xLocation > numberOfColumns]) ifTrue: [^self].
(yLocation < 1 or: [yLocation > numberOfLines]) ifTrue: [^self].
self changed: y.
x _ xLocation.
y _ yLocation!
scrollBy: aNumber
"Scroll up the receiver aNumber lines. Override to add functionality
for emphasis."
super scrollBy: aNumber.
aNumber timesRepeat: [
emphasis removeFirst.
emphasis addLast: (ByteArray new: numberOfColumns withAll: 0)].! !
!IntelligentEmulator methodsFor: 'private'!
resetDefaults
"Reset the default parameters"
autoLineFeed _ false.
autoMargin _ true.
displayMode _ 0. "Normal display"! !
IntelligentEmulator subclass: #VS100Emulator
instanceVariableNames: 'state parameters currentParam '
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
VS100Emulator comment:
'I represent a model of a VS100 (DEC) terminal. I also provide a reasonable
imitation of several other ''ANSI'' terminals, including VT100s.
Instance variables:
state This is the state variable for the finite state machine used to
interpret the incoming character stream.
parameters An Array of Integers, used to hold the numeric parameters
(up to 8) required by ANSI terminals.
currentParam An Integer, representing the current parameter. Used as an
index into the parameters array.
'!
!VS100Emulator methodsFor: 'initialize-release'!
initialize
"Initialize the state variable."
super initialize.
self endOfSequence! !
!VS100Emulator methodsFor: 'character handling'!
addToParameter: char
"The parameter char is a digit. Add it to the current parameter."
| param |
param _ parameters at: currentParam.
parameters at: currentParam put: (param * 10 + char digitValue)!
displayCharacter: char
"Interpret incoming characters. A simple state machine is
implemented using the instance variable state."
(state = 0) ifTrue: [^self processState0: char].
(state = 1) ifTrue: [^self processState1: char].
(state = 2) ifTrue: [^self processState2: char].
(state = 3) ifTrue: [^self processState3: char].
self error: 'invalid state - this can''t happen'!
endOfSequence
"Clean up after the end of an escape sequence."
state _ 0.
parameters _ Array new: 8 withAll: 0.
currentParam _ 1!
processState0: char
"Currently, we are in state 0. Decide what to do on the
basis of the parameter char."
(char = Character esc)
ifTrue: [^state _ 1]
ifFalse: [^super displayCharacter: char]!
processState1: char
"Currently, we are in state 1. Decide what to do on the
basis of the parameter char."
char = $[ ifTrue: [^state _ 2].
char = $M ifTrue: [
self cursorUp: 1.
^self endOfSequence].
char = $D ifTrue: [
self cursorDown: 1.
^self endOfSequence].
^self doNothing!
processState2: char
"Currently, we are in state 2. Decide what to do on the
basis of the parameter char."
char = $; ifTrue: [^currentParam _ (currentParam + 1) min: 8].
char isDigit ifTrue: [^self addToParameter: char].
char = $@ ifTrue: [^self insertCharacters].
char = $A ifTrue: [^self cursorUp].
char = $B ifTrue: [^self cursorLeft].
char = $C ifTrue: [^self cursorRight].
char = $D ifTrue: [^self cursorDown].
char = $H ifTrue: [^self move].
char = $J ifTrue: [^self clearDisplay].
char = $K ifTrue: [^self clearLines].
char = $L ifTrue: [^self addLines].
char = $M ifTrue: [^self deleteLines].
char = $P ifTrue: [^self deleteCharacters].
char = $m ifTrue: [^self displayMode: (parameters at: 1)].
char = $r ifTrue: [^self resetDefaults].
char = $? ifTrue: [^state _ 3].
^self doNothing!
processState3: char
"Currently, we are in state 3. Decide what to do on the
basis of the parameter char."
char = $; ifTrue: [^currentParam _ (currentParam + 1) min: 8].
char isDigit ifTrue: [^self addToParameter: char].
char = $l ifTrue: [
(parameters at: 1) = 7 ifTrue: [self autoMargin: false].
^self doNothing].
char = $h ifTrue: [
(parameters at: 1) = 7 ifTrue: [self autoMargin: true].
^self doNothing].
^self doNothing! !
!VS100Emulator methodsFor: 'display manipulation'!
addLines
"Add the appropriate number of blank lines at the position
indicated by the cursor."
self addLines: ((parameters at: 1) max: 1).
self endOfSequence!
clear
"Clear the entire display."
super clear.
self changed: #clear.
self endOfSequence.!
clearDisplay
"Clear some part of the display."
(parameters at: 1) = 0 ifTrue: [^self clearToEndOfDisplay].
(parameters at: 1) = 1 ifTrue: [^self clearFromBeginningOfDisplay].
(parameters at: 1) = 2 ifTrue: [^self clear]!
clearEntireLine
"Override to ensure correct reseting of the state machine."
super clearEntireLine.
self endOfSequence!
clearFromBeginningOfDisplay
"Override to ensure clean reset of the state machine."
super clearFromBeginningOfDisplay.
self endOfSequence!
clearFromBeginningOfLine
"Override to ensure correct reseting of the state machine."
super clearFromBeginningOfLine.
self endOfSequence!
clearLines
"Clear some part of the current line, as indicated by the first parameter."
(parameters at: 1) = 0 ifTrue: [^self clearToEndOfLine].
(parameters at: 1) = 1 ifTrue: [^self clearFromBeginningOfLine].
(parameters at: 1) = 2 ifTrue: [^self clearEntireLine]!
clearToEndOfDisplay
"Override to ensure clean reset of the state machine."
super clearToEndOfDisplay.
self endOfSequence!
clearToEndOfLine
"Override to ensure correct reseting of the state machine."
super clearToEndOfLine.
self endOfSequence!
cursorDown
"Move the cursor down the appropriate number of lines, unless the
cursor would overflow at the bottom."
self cursorDown: ((parameters at: 1) max: 1).
self endOfSequence!
cursorLeft
"Move the cursor left (in a non-destructive manner) the
appropriate number of places, except when the cursor
would overflow at the left-hand margin."
self cursorLeft: ((parameters at: 1) max: 1).
self endOfSequence!
cursorRight
"Move the cursor right (in a non-destructive manner) the
appropriate number of places, except when the cursor
would overflow at the right-hand margin."
self cursorRight: ((parameters at: 1) max: 1).
self endOfSequence!
cursorUp
"Move the cursor up the appropriate number of lines, unless the cursor
would overflow at the top."
self cursorUp: ((parameters at: 1) max: 1).
self endOfSequence!
deleteCharacters
"Delete a number of character spaces, as indicated by the first parameter."
((parameters at: 1) max: 1) timesRepeat: [self deleteCharacter].
self endOfSequence!
deleteLines
"Delete the appropriate number of lines at the position
indicated by the cursor."
self deleteLines: ((parameters at: 1) max: 1).
self endOfSequence!
displayMode: anInteger
"Override to ensure correct reseting of the state machine."
super displayMode: anInteger.
self endOfSequence!
doNothing
"Override the superclass in order to reset the state variable."
super doNothing.
self endOfSequence!
insertCharacters
"Insert a number of character spaces, as indicated by the first parameter."
((parameters at: 1) max: 1) timesRepeat: [self insertCharacter].
self endOfSequence!
move
"Move to the locations indicated by the first and second parameters."
self moveToX: ((parameters at: 2) max: 1) y: ((parameters at: 1) max: 1).
self endOfSequence! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
VS100Emulator class
instanceVariableNames: ''!
!VS100Emulator class methodsFor: 'instance creation'!
openShell
"VS100Emulator openShell."
IntelligentEmulatorView
openOn: (self getTerminal)
label: 'Small VS100'!
openShell: aNumber
"VS100Emulator openShell: 1."
IntelligentEmulatorView
openOn: (self getTerminal: aNumber)
label: 'Small VS100'! !
TermEmulatorView subclass: #IntelligentEmulatorView
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
IntelligentEmulatorView comment:
'I add the functionality which knows how to display characters with
various emphasis types. At present, only ''reverse video'' emphasis is
supported.
'!
!IntelligentEmulatorView methodsFor: 'displaying'!
reallyDisplayLine: aNumber
"Override the method in the superclass, so that we can deal with
highlighting."
| array refPoint pos start highLight |
super reallyDisplayLine: aNumber.
array _ model emphasisAt: aNumber.
refPoint _ insetDisplayBox topLeft + (-3@(aNumber - 1 * CharHeight + 2)).
pos _ 0.
highLight _ false.
[pos _ pos + 1. pos <= model numberOfColumns] whileTrue: [
((array at: pos) > 0 and: [highLight not]) ifTrue: [
highLight _ true.
start _ pos].
((array at: pos) = 0 and: [highLight]) ifTrue: [
highLight _ false.
Display reverse: ((start* 7)@0 + refPoint
extent: (((pos - start)*7)@(CharHeight - 2)))].
((pos = model numberOfColumns) and: [highLight]) ifTrue: [
Display reverse: ((start* 7)@0 + refPoint
extent: (((pos - start + 1)*7)@(CharHeight - 2)))]]! !
MouseMenuController subclass: #TermEmulatorController
instanceVariableNames: ''
classVariableNames: 'SavedInterruptKey '
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
TermEmulatorController comment:
'I represent the controller for a simple terminal emulator.
'!
!TermEmulatorController methodsFor: 'initialize-release'!
initialize
super initialize.
self initializeYellowButtonMenu!
release
"Overridden to allow some necessary clean-up by TermEmulators."
super release.
model release! !
!TermEmulatorController methodsFor: 'basic control sequence'!
controlInitialize
"Save the key that interrupts the system and install a different
one so I can have a different meaning for control c."
SavedInterruptKey _ InputState interruptKey.
InputState interruptKey: 162. "L3 key"
^super controlInitialize!
controlTerminate
"Return the interrupt key to its saved value."
InputState interruptKey: SavedInterruptKey.
^super controlTerminate! !
!TermEmulatorController methodsFor: 'control defaults'!
controlActivity
"Determine whether the user pressed the keyboard. If so,
read the keys."
sensor keyboardPressed
ifTrue: [self readKeyboard]
ifFalse: [super controlActivity]!
isControlActive
^(view containsPoint: sensor cursorPoint) & sensor blueButtonPressed not! !
!TermEmulatorController methodsFor: 'menu messages'!
reset
"Reset the terminal port (useful if something has gone wrong)."
model reset! !
!TermEmulatorController methodsFor: 'keyboard input'!
readKeyboard
"Sends keyboard characters to the model (a TermEmulator)."
| buffer |
buffer _ WriteStream on: (String new: 200).
[sensor keyboardPressed] whileTrue: [buffer nextPut: sensor keyboard].
(model sendAll: buffer contents) ifFalse: [view flash].! !
!TermEmulatorController methodsFor: 'private'!
initializeYellowButtonMenu
"Sets up our yellow button commands."
self yellowButtonMenu:
(PopUpMenu labelList: #((reset)))
yellowButtonMessages: #(reset)! !
VS100Emulator subclass: #LargeVS100Emulator
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
LargeVS100Emulator comment:
'I represent a ''large'' VS100 terminal, which has 65 lines of 80 columns.
'!
!LargeVS100Emulator methodsFor: 'private'!
initializeLinesAndColumns
"The default number of lines and columns are set up here."
self setLines: 65.
self setColumns: 80.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
LargeVS100Emulator class
instanceVariableNames: ''!
!LargeVS100Emulator class methodsFor: 'instance creation'!
openShell
"LargeVS100Emulator openShell."
IntelligentEmulatorView
openOn: (self getTerminal)
label: 'Large VS100'!
openShell: aNumber
"LargeVS100Emulator openShell: 1."
IntelligentEmulatorView
openOn: (self getTerminal: aNumber)
label: 'Large VS100'! !
IntelligentEmulator subclass: #NewburyEmulator
instanceVariableNames: 'state firstParam '
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-TerminalEmulator'!
NewburyEmulator comment:
'I represent a Newbury 7001/7003 terminal (Ugh!!).
Instance variables:
state A state variable used by the finite state machine which
interprets the incoming character stream.
firstParam The first numeric parameter supplied when a cursor move
operation is specified.
'!
!NewburyEmulator methodsFor: 'initialize-release'!
initialize
"Initialize the state variable."
super initialize.
self endOfSequence! !
!NewburyEmulator methodsFor: 'character handling'!
displayCharacter: char
"Interpret incoming characters. A simple state machine is
implemented using the instance variable state."
(state = 0) ifTrue: [^self processState0: char].
(state = 1) ifTrue: [^self processState1: char].
(state = 2) ifTrue: [^self processState2: char].
self error: 'invalid state - this can''t happen'!
endOfSequence
"Clean up after the end of a cursor positioning sequence."
state _ 0!
processState0: char
"Currently, we are in state 0. Decide what to do on the
basis of the parameter char."
char isAlphaNumeric ifTrue: [^super displayCharacter: char].
(char = 1 asCharacter) ifTrue: [^self addLine].
(char = 2 asCharacter) ifTrue: [^self deleteLine].
(char = 11 asCharacter) ifTrue: [^self cursorUp: 1].
(char = 15 asCharacter) ifTrue: [^self deleteCharacter].
(char = 16 asCharacter) ifTrue: [^self insertCharacter].
(char = 18 asCharacter) ifTrue: [^self displayMode: 1].
(char = 19 asCharacter) ifTrue: [^self displayMode: 0].
(char = 20 asCharacter) ifTrue: [^self displayMode: 1].
(char = 22 asCharacter) ifTrue: [^state _ 1].
(char = 24 asCharacter) ifTrue: [^self cursorRight: 1].
(char = 25 asCharacter) ifTrue: [^self clearToEndOfLine].
(char = 29 asCharacter) ifTrue: [^self home].
(char = 31 asCharacter) ifTrue: [
self clear.
^self changed: #clear].
^super displayCharacter: char!
processState1: char
"Currently, we are in state 1. Decide what to do on the
basis of the parameter char."
firstParam _ char asciiValue - 31.
state _ 2!
processState2: char
"Currently, we are in state 2. Decide what to do on the
basis of the parameter char."
self moveToX: firstParam y: (char asciiValue - 31).
self endOfSequence! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
NewburyEmulator class
instanceVariableNames: ''!
!NewburyEmulator class methodsFor: 'instance creation'!
openShell
"NewburyEmulator openShell."
IntelligentEmulatorView
openOn: (self getTerminal)
label: 'Newbury'!
openShell: aNumber
"NewburyEmulator openShell: 1."
IntelligentEmulatorView
openOn: (self getTerminal: aNumber)
label: 'Newbury'! !